perm filename FINGER.SAI[F,ACT]14 blob sn#374709 filedate 1978-08-22 generic text, type C, neo UTF8
COMMENT ⊗   VALID 00014 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00003 00002	begin "finger" COMMENT:  must be loaded using the /NOSAISEG switch
C00010 00003	require "files[f,act]" source_file
C00016 00004	!			Useful Sail macros
C00018 00005	!			General I/O
C00022 00006	!			General procedures
C00025 00007	!			break tables
C00027 00008	begin "main"		! SORT, NETGRAPH
C00029 00009	procedure SHOWJOBS  begin 	! this outputs job information
C00035 00010				! Show people who are not logged in
C00038 00011	external integer procedure NETFNG(string command,site)  ! network Finger
C00042 00012	procedure NAMED(string lst)	begin	! Identify a list of persons
C00050 00013	procedure RUNNING	begin		! show everyone who is running
C00051 00014				! main program
C00067 ENDMK
C⊗;
begin "finger" COMMENT:  must be loaded using the /NOSAISEG switch
*18 Jan 1978	Licking FINGER	Les

			NETWORK FINGER
A FINGER command containing %<site name> will now attempt to finger people
at other Arpanet sites.  It does this by connecting to the FINGER socket
at the specified site and passing the rest of whatever you typed (before
and after the "%<site name>" to the host.  If that host supports Network
Finger, then you get whatever they return.

For example, "FING TK%AI" tells you about Tom Knight at MIT-AI and
"FING %SRI" tells you about everyone who is running on SRI-KL.  At this
writing, only the following sites respond to a network FINGER:
all MIT ITS sites (ai, mc, ml, dm), sri-kl, sri-ka, and office-1.
More will be joining shortly.

Normally only one site can be specified in a single FINGER command, but if
you would like to waste some time, say "FING %*" and it will tell you
about everyone out there.

			DOMESTIC FINGER
The system command "FING" shows data on all jobs, in order by programmer
initials.  The "IDLE" column shows the time, in minutes, since the given
job was last in the RUN queue.  If the job is currently in the STOP or
NULL queues, a "." follows.

If there is a digit in the next column, it represents the number of extra
Data Disc channels that belong to this job.

Finally, the "Terminal" part shows the location of the owner (the terminal
that last typed something at this job).  "detached", of course means just
that.  "disowned" means that the terminal that last owned this line has
released it.  "TV" means that this is a television (Data Disc) terminal
that is displaying the channel currently.  "tv" means that the terminal
that owns this job isn't looking at it.

If terminals other than the owner are viewing this job's main channel,
then they are listed on subsequent lines, with the job field blank.  If
you want to know the TTY# rather than the physical terminal, use WHERE or
WHO rather than FINGER.

			   POINTING THE FINGER
The command "FING <people list>" shows data only on the specified people.
For example, "FING JMC,DAVE,WILL" requests information on programmer JMC
and anyone whose first or last name begins with "DAVE" or "WILL".
String matching uses the following precedence:
  1) exact match on programmer initials,
  2) exact match on friendly or last names,
  3) match on leading characters of friendly or last names.
If a given string matches more than one person at a given level, it
reports "ambiguous" and lists their names.

If only one person is specified and he is not logged in, it normally tells
when he last logged out and shows his plan file, if any, but this can be
suppressed with switches (see below).

			FILE LISTS
Arguments in the FINGER command are separated by commas and/or spaces.
An argument of the form "@<file name>" causes that file to be read.
Files can include references to other files, ad nauseum.  In files,
everything to the right of a semicolon on a given line is ignored,
so that comments can be put there.

The default file extension is "DIS" and the default PPN is "[P,DOC]".
Thus if you say "FING @H", it will first look for a file in you area
called "H".  If that doesn't exist, it will next try "H.DIS" in your
area and, if necessary, "H.DIS[P,DOC]", the latter being the list of
hand-eye people which is kept in [P,DOC] along with other group lists
(see SAIL Telephone Directory).

			SWITCHES
Normally, if only one person is specified in the FINGER command and he is
not logged in, the time of his last logout and plan file, if any, are
given.  This printout can be suppressed by using the "-LOGOUT" or "-PLAN"

You can force printing of last logout or plan files even for lists of
people by using the "/LOGOUT" or "/PLAN" switches, which can also be
abbreviated to one letter.  Thus "FING @VB/L" lists everyone on the
volleyball list who is logged in and, for the rest,  the time of their
last logout.

			DOCUMENTATION
The command "FINGER ?" will cause this description to be printed out.
There is also a copy in FINGER.LES[UP,DOC].
;
require "files[f,act]" source_file;
require "[]<>" delimiters;	define !=[Comment];

define debug=[false];	! if TRUE then BAIL is in and no safe arrays;
define ddmin=['66];	! lowest numbered DD line;
define linemax=['157];	! max. physical line number;
define pnmax=[200];	! max. # of programmers on project list;
define tmpcormax=[16];	! max. tmpcor file size;
define docfile=["finger.les[up,doc]"];	! location of documentation file;
!			Useful Sail macros;
define TAB=[(""&'11)],LF=[(""&'12)],VT=[(""&'13)],FF=[(""&'14)],CR=[(""&'15)],
    ALT=[(""&'175)],DEL=[(""&'177)],↓=[(CR&LF)],THRU=[step 1 until],
    LN=[length], PROC=[simple procedure], SAY=[outstr],ttyuuo=['51000000000],
    EXIT=[quick_code calli 1,'12; calli '12 end];
define blanks=[                                        ];
redefine blanks=["]&cvms(blanks)&cvms(blanks)&cvms(blanks)&cvms(blanks)&["];
define	INLINE=[input(inch,inlf)];	! inputs one line, omitting CRLF;
define	INFORM=[input(inch,inff)];	! inputs to next form feed;

define symbrk=0;		! for generating symbols;
define BREAK_TABLE(table,term,omit,modes)=[
	redefine symbrk=symbrk+1,  zzz=[break]&cvs(symbrk);
	simple procedure zzz;  setbreak(table←getbreak,term,omit,modes);
	require zzz initialization;
	];
define break(id,term,omit,modes)= [
	integer id;
	break_table(id,term,omit,modes);
	];
define scnbrk(id,term,omit,modes)= [
	redefine qqq=[tableno]&cvs(symbrk);
	integer qqq;
	define id(s)=[scan(s,]&cvms(qqq)&[,brk)];
	break_table(qqq,term,omit,modes);
	];

define letters=["ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"];

!			General I/O;
internal integer inch,ouch,brk,eof,inlf,inff;	! input/output globals;

proc PREP0;  BEGIN 				! initialize things;
    setbreak(inlf←getbreak,LF,CR,"INS");
    setbreak(inff←getbreak,FF,NULL,"INS");
    end;
require prep0 initialization;

string proc ask(string s);  begin outstr(s);  return(inchwl)  end;

proc OOPS(string mess);
    begin print(↓,mess,↓); call(0,"RESET"); exit; end;

string proc look(string file);  begin
! does an open and lookup on a text file and delivers the first line,
ignoring the TV/E directory,if any;
    string lin; boolean fl;
    open(inch←getchan,"DSK",1,19,0,400,brk,eof);
    lookup(inch,file,fl);
    if fl then begin release(inch); return(del) end;
    lin←inline;
    if equ(lin[1 to 9],"COMMENT ⊗") then begin "flush directory"
	do inform until brk=ff;
	return(inline);
	end;
    return(lin)
    end "LOOK";
string proc lookout(string file);	begin	string ss;
	if ¬equ(ss←look(file),del) then return(ss) else oops(file&" not found"&↓);
	end;

string proc LEFT(integer L; string S);
    return(if ln(S)<L then S&blanks[1 to L-ln(S)] else S[1 to L]);

proc LPRINT(integer L; string S);
    if ln(S)<L then print(S,blanks[1 to L-ln(S)]) else print(S[1 to L]);

proc RPRINT(integer L; string S);
    if ln(S)<L then print(blanks[1 to L-ln(S)],S) else print(S[∞-L+1 to ∞]);

!			General procedures;
ifc debug thenc define safer=[ ]; elsec
    define safer=[safe];  endc

PRELOAD_WITH "January", "February", "March", "April", "May", "June",
	"July", "August", "September", "October", "November", "December";
STRING SAFER ARRAY MONTH[1:12];

STRING PROC DATE(INTEGER D);	! ((year-1964)*12+month-1)*31+day-1;
	RETURN(CVS(D MOD 31+1)&" "&MONTH[(D←D DIV 31) MOD 12 +1][1 to 3]&
	    " "&CVS(D DIV 12 + 1964));

safer integer array buf[1:tmpcormax];			! tmpcor file buffer;
boolean procedure TMPCRD(integer filejob);	begin	! read tmpcor file;
	safe own integer array addr[0:2];
	integer adrloc;
	external integer _skip_;
	
	if adrloc=0 then start_code "initialize"
		protect_acs 2;
		move 2,buf;
		subi 2,1;
		hrli 2,-tmpcormax;		! 1=[iowd tmpcormax,,buf[1]];
		movem 2,access(addr[1]);
		move 2,addr;
		hrli 2,1;
		movem 2,adrloc;
		end;
	addr[0]←filejob;
	call(adrloc,"tmpcrd");
	return(_skip_);
	end "TMPCRD";

define fetch(addr)=[memory['400000+addr]];

integer jbtlin,jobmax,jbtsts,prjprg;	! see SETUP on last page;

boolean proc active(integer job);	begin		! TRUE if job is active;
	integer status;
	define jna=['40000000000];	! job # assigned bit in jbsts;
	define jlog=['10000000000];	! job logged in bit in jbsts;
	define jseg=['1000000000];	! upper segment bit in jbsts;

	return((status←fetch(jbtsts+job))land jna ∧
	    (fetch(jbtlin+job)≠-1 ∨ (status land jlog) ∧ ¬(status land jseg)));
	end "ACTIVE";

integer proc getpn(integer job);	begin	! get PN for job & left justify;
	integer pno;
	return(if (pno←fetch(prjprg+job)land '777777) land '770000 then pno
	    else pno lsh (if pno land '7700 then 6 else 12));
	end;

external integer procedure TTYLOC(integer jobno);  ! PTY location;
!			break tables;
scnbrk(totab,"	",null,"insk");
scnbrk(tosp," ",null,"insk");
scnbrk(flush,<";, 	">,null,"xnr");
scnbrk(tosemi,<";">,null,"ins");
scnbrk(tonolet,letters,null,"xr");
scnbrk(toletdig,<letters&"0123456789*">,null,"inr");
scnbrk(toamp,"&",null,"is");
scnbrk(tofile,<".[, &%(-/@	">,null,"inr");
scnbrk(torb,<"] ">,null,"ins");
scnbrk(tocomma,<",">,null,"is");
scnbrk(tocrlf,lf,null,"ina");
scnbrk(topercent,<"@%(">,null,"is");
scnbrk(todelim,<" ,	/">,null,"ikr");

safer string array loc[0:linemax+1];      ! locations of terminals;
safer integer array ddchan[ddmin:linemax]; ! main DD channel for line;
safer integer array vdsmap[ddmin:linemax]; ! Video switch map;

			! Initialization;
call('377777000000,"setpr2");	! make monitor = second segment;
jbtlin←fetch('236);		! location of line number table;
jobmax←fetch('222);		! highest possible job number;
jbtsts←fetch('210);		! location of job status table;
prjprg←fetch('211);		! location of project-programmer table;

begin "main"		! SORT, NETGRAPH;
safer integer array job,pn[1:jobmax];	! job #, PN;
safer string array name[1:jobmax];	! programmer name table;
integer users;				! # of active jobs;

procedure SORT;	begin   ! bubble sort active jobs by PN;
	integer ji,sin;
	boolean sorted;
	sin←users;
	do begin "bubble sort"
		sorted←true;    sin←sin-1;
		for ji←1 thru sin do if pn[ji]>pn[ji+1] then begin
			pn[ji]↔pn[ji+1];  job[ji]↔job[ji+1];
			name[ji]↔name[ji+1];  sorted←false;
			end;
		end "bubble sort"
	    until sorted;
	end "SORT";

proc NETGRAPH(integer jb,pty);  begin   ! network graphics site;
	integer ngi,nps;
	if tmpcrd(cvsix("net")+jb) then for ngi←1 thru tmpcormax do
	    if (nps←buf[ngi])=0 then done else
	    if (nps lsh -24)=pty then begin "site name"
		string ns;
		ns←cvxstr(nps);  print(ns[3 to 6]);
		return
		end;
	print("??");
	end "NETGRAPH";
procedure SHOWJOBS;  begin 	! this outputs job information;
	safer integer array exchan[1:jobmax];	! extra channels used by job;

	integer pi,pj,ptyjob,ftime,cdate,ctime,jobnam,jobque,oldie,ownbyt;

	print("     Person          Job Jobnam Idle    Terminal"&↓);
	sort;
	loc[0]←lookout(roomfile);	! This file gives rooms for tty lines;
	for pi←1 thru linemax+1 do loc[pi]←inline;
	release(inch);

	for pi←0 thru 31 do begin "ddchan"	integer use,priv;
		if (use←(priv←call('200+pi,"ddchan")lsh-18)land '377) then
		    if use<'100 then exchan[use]←exchan[use]+1
		    else if use<'200 then
			ddchan[use-('100-ddmin)]←if priv land '400000 then -pi else pi;
							! - means hidden;
			! main channel for job;
		end "ddchan";
	for pi←ddmin thru linemax do vdsmap[pi]←call(('200000+pi)lsh 18,"vdsmap");

	ownbyt←fetch('333)+'400000;	! byte pointer to owning KBD table;
	ptyjob←fetch('270)-(linemax+2);	! location of pty superior job table;
	jobnam←fetch('225);		! location of job name table;
	jobque←fetch('231);		! location of job queue table;
	ftime←fetch('274);		! location of date,,seconds since run;
	cdate←call(0,"date") lsh 18;	! current date in left half;
	ctime←call(0,"timer")%60;	! seconds since midnight;

	oldie←0;
	for pi←1 thru users do begin "printout"
		integer prog,lr,tim,ptl,line;	string ss;

		setformat(2,0);
		pj←job[pi];	prog←pn[pi];
		if oldie=prog then print(blanks[1 to 22]) else begin "new guy"
			string ns;  integer ppn;
			oldie←prog;
			if ln(ns←name[pi]) then lprint(22,ns) else
			    if (ppn←pn[pi])=cvsix("   100") then
			    print("100 not logged in     ") else begin "unknown"
				ns←cvxstr(ppn);
				print(ns[4 to 6]," UNKNOWN           ");
				end;
			end "new guy";
		print(pj," ",cvxstr(fetch(jobnam+pj))," ");
		tim←fetch(ftime+pj);	! time since last run;
		lr←((if cdate=(tim land ('777777 lsh 18)) then 0 else 86400) +
		    ctime -(tim land '777777))div 60;
		if lr≤0 then print("   ") else if lr>999 then print("***") else
		    rprint(3,cvs(lr));
				! "." if in STOP Q or NULLQ;
		print(if '11≠fetch(jobque+pj)≠'10 then " " else ".");

		setformat(0,0);
		print(if line←exchan[pj] then cvs(line) else " ");
		if (line←fetch(jbtlin+pj))=-1 then print("detached"&↓) else
		    if (line land ('4000 lsh 18)) then begin "PTY"
			lprint(13,"PTY"&cvos(ptl←line land '377));
			if (lr←fetch(ptyjob+ptl))=0 then print("ORPHAN")
			  else begin "superior job"
			    integer sjob;
			    if (ttyloc(lr) ≠ 0) then begin
			      ss←cvxstr(sjob←fetch(jobnam+lr));
			      print("job ",lr," ",ss);
			      if (sjob land '777777)=cvsix("   GRF") then begin
				print(" from "); netgraph(lr,ptl); end;
			      end;
			    end "superior job";
			print(↓);
			end "PTY"
		    else if (line←line land '177)<ddmin ∨ line>linemax then
			print(loc[line][1 to 43],↓)
		    else begin "DD"
			integer dd,dc,di;
			dc←(1 lsh 35) lsh - abs ddchan[line]; ! map bit for DD;
			dd←ldb(ownbyt+line);	! KBD that owns this line;
			print(if dd='12 then "disowned" else
			    if VDSMAP[dd] land dc then loc[dd][1 to 43] else
			    "tv"&loc[dd][3 to 43],↓);
			for di←ddmin thru linemax do if dc land vdsmap[di] ∧
			  di≠dd then begin
			    lprint(37,if ddchan[line]<0 then
			      "        *** SPY *** SPY *** SPY ***" else "");
			    print(loc[di][1 to 43],↓);
			    end;
			end "DD";
		end "printout";
	end "SHOWJOBS";
			! Show people who are not logged in;
procedure NIX(integer count; integer array npn; string array nname; boolean noplan);
    begin
	safer integer array datime[1:count];	! time(s) of last logout;
	boolean flag;
	integer ni;

	arrclr(datime,-1);		! set to -1;
	open(inch←getchan,"dsk",'10,19,0,400,brk,eof);
	lookup(inch,"  1  1.ufd[1,1]",flag);
	! mfd format: [0] <ppn(36)>  [1] "UFD",,<hi date (3)><other (15)>
	    [3] <protect (9)><mode (4)><minutes (11)><lo date (12)>
	    [4:15] <junk (36)>;

	do begin "search"
		integer pno,si;
		safer own integer array mfd[0:15];

		arryin(inch,mfd[0],16);		! read an MFD entry;
		pno←mfd[0] land '777777;
		for si←1 thru count do if pno=npn[si] then begin "got one"
			datime[si]←datime[si] max
			    (((mfd[1] land '700000) lsh 15) lor
			    ((mfd[2] land '7777) lsh 18) lor
			    ((mfd[2] land '37770000) lsh -12));	! date,,time;
			done;
			end;
		end "search"
	    until eof;
	release(inch);
	for ni←1 thru count do begin "typout"
		integer dat;	string ns;

		lprint(22,nname[ni]);
		if (dat←datime[ni])=-1 then print(" -- no file areas"&↓)
		    else begin "logout"
			if dat=0 then print("a long time ago") else begin "date"
			    integer time;
			    setformat(2,0);
			    print((time←dat land '3777)%60,":");
			    setformat(-2,0);
			    print(time mod 60," on ");
			    setformat(0,0); print(date(dat lsh -18));
			    end "date";
			if noplan then print(↓) else
			if (ns←look(cvxstr(npn[ni])&".pln[2,2]"))=del then
			    print(".  No plan."&↓) else begin "plan"
				print(".  Plan:"&↓);
				do begin print("  ",ns,↓);  ns←inline; end
				    until eof;
				print(↓);
				end;
			release(inch);
			end "logout";
		end "typout";
	end "NIX";
external integer procedure NETFNG(string command,site);  ! network Finger;
require "NETFNG" load_module;		! all this courtesy of MRC;
procedure NETWORK(string before,after);	begin ! do a network finger;
    string host;
    toletdig(after);			! flush everything up to site name;
    host←todelim(after);
    if host≠"*" then netfng(before&after&↓,host) else begin "survey"
	for host←"SU-AI", "SRI-KL","SRI-KA","OFFICE-1","MIT-AI","MIT-MC","MIT-ML",
	  "MIT-DMS" do begin print(↓&"site: ",host,↓);
          netfng(before&after&↓,host); end;
	end "survey";
    exit;
    end "NETWORK";
procedure NAMED(string lst);	begin	! Identify a list of persons;
    safer string array handle[1:pnmax];     ! names to be found;
    integer hi;                             ! # of people on list;
    integer nologout,noplan; ! -1=suppress, +1=show logout & plan;
    string rs;

    rs←toamp(lst);
    while ln(lst) do begin "read file"
	string file,ext,ppn,line;
	toletdig(lst);                  ! remove "&" and leading blanks;
	file←tofile(lst);               ! file name up to "." or "[";
	ext←if brk="." then lop(lst)&tofile(lst) else null;
	if brk≠"[" then ppn←null else begin "ppn"
	    string pj;
	    ppn←torb(lst);	pj←tocomma(ppn);	flush(ppn);
	    ppn←pj&","&(if ln(ppn) then ppn else
	      cvxstr(call(0,"dskppn"))[4 to 6])&"]";
	    end "ppn";
	if (line←look(file&ext&ppn))=del ∧
	    (ln(ext) ∨ (line←look(file&".dis"&ppn)) = del) ∧
	    (ln(ppn) ∨ (line←look(file&".dis[p,doc]")) = del) then
	    oops(file&ext&ppn&" file not found");
	while ¬eof do begin "read"
	    rs←rs&","&tosemi(line);
	    line←inline;
	    end;
	release(inch);
	if ln(rs)>(4*pnmax) then oops("Too many people");
	rs←rs&","&toamp(lst);
	end "read file";
    lst←topercent(rs);		! check for network finger;
    if ln(rs) then network(lst,rs);	! do a network finger;
    flush(lst);
    hi←nologout←noplan←0;
    do begin "scan list"
	integer op;
	if (op←lst)="-" ∨ op="/" then begin "switches"
	    string switch;  integer ls;
	    toletdig(lst);          ! remove "-", "/" & leading blanks;
	    switch←tonolet(lst);
	    if equ(switch,"LOGOUT"[1 to ls←ln(switch)]) then
		nologout←(if op="-" then -1 else 1) else
		if equ(switch,"PLAN"[1 to ls]) then
		noplan←(if op="-" then -1 else 1) else
		oops("Undefined switch: "&switch);
	    end "switches"
	  else begin "string"
	    if (hi←hi+1)>pnmax then oops("List too long");
	    handle[hi]←tonolet(lst);
	    end;
	flush(lst);
	end
      until ln(lst)=0;
    if hi=0 then oops("Null list");

    begin "search"
    safer integer array state[1:hi];   ! 0 = unknown, 2 = substring match,
	    3 = ambig. substring match, 4 = exact match, 5 = ambig. match,
	    6 = PN match,   8 = logged in;

    safer integer array npn[1:hi];                  ! PNs found;
    safer string array nname[1:hi];                 ! names found;
    string line;
    integer ji,jj,statlo;

    line←lookout(prgfile);          ! read file of PN<tab>names;
    do begin "matchup"
	integer si,stati;
	string fpn,friend,last,mh;

	proc namehim(integer ni); begin ! store state, etc.;
	    if ni=(stati land '16) then begin "ambiguous"
		state[si]←ni+1;
		npn[si]←0;              ! clear PN;
		nname[si]←nname[si]&↓&left(4,fpn)&line;
		end
	      else begin "OK"
		state[si]←ni;
		npn[si]←cvsix("   "&fpn);
		nname[si]←left(4,fpn)&line;
		end;
	    statlo←statlo min ni;
	    end;

	fpn←totab(line);  friend←tosp(last←line);
	last←totab(last);                       ! upper case-ify;
	statlo←6;
	for si←1 thru hi do if (stati←state[si])<6 then begin "try"
	    if equ(fpn,mh←handle[si]) then namehim(6)
		else if equ(mh,last) ∨ equ(mh,friend) then namehim(4)
		else if stati≤3 ∧ (equ(mh,last[1 to ln(mh)]) ∨
		    equ(mh,friend[1 to ln(mh)])) then namehim(2)
		else statlo←statlo min stati;
	    end "try";
	end "matchup"
    until ln(line←inline)=0 ∨ statlo=6;
    release(inch);

    for ji←1 thru hi do if (jj←state[ji])=0 then begin "not found"
	string js;
	if 2≤ln(js←handle[ji])≤3 then begin "outlaw?"
		npn[ji]←cvsix("   "&js);  nname[ji]←left(4,js)&"UNKNOWN";
		end
	    else begin
		print("""",handle[ji],""" unrecognized"&↓);
		state[ji]←8;            ! mark it "finished";
		end;
	end
    else if (jj land 1)=1 then begin "ambiguous";
	print("""",handle[ji],""" is ambiguous:"&↓,nname[ji],↓);
	state[ji]←8;                    ! we're done with it;
	end;

    users←0;
    for ji←1 thru jobmax do if active(ji) then begin        ! get PPN;
	integer pno;
	pno←getpn(ji);
	for jj←1 thru hi do if pno=npn[jj] then begin "hit"
	    job[users←users+1]←ji; pn[users]←pno;
	    name[users]←nname[jj]; state[jj]←8;
	    end;
	end;

    if users then showjobs;                 ! output people logged in;
    if hi>1 ∧ nologout<1 ∧ noplan<1 ∨ nologout=-1 then	! suppress the rest?;
	if users=0 then oops("None logged in.") else exit;

    jj←0;
    for ji←1 thru hi do if state[ji]≠8 then begin "check state"
	integer pno,ci;
	label skip;

	if ((pno←npn[ji])land '77)=0 then
	    pno←pno lsh (if pno land '7777 then -6 else -12);
	for ci←1 thru jj do if pno=npn[ci] then go to skip;
	nname[jj←jj+1]←nname[ji];       ! do if not a duplicate;
	npn[jj]←pno;
skip:   end;
    if jj then begin
	print(if users then ↓&"------------              Last logout"&↓ else
	    "     Person               Last logout"&↓);
	nix(jj,npn,nname,hi>1 ∧ noplan<1 ∨ noplan<0);	! find last login;
	end;
    end "search";
    end "NAMED";
procedure RUNNING;	begin		! show everyone who is running;
	integer ri,rpn;
	string line;

	users←0;
	for ri←1 thru jobmax do if active(ri) then begin "active"
		job[users←users+1]←ri;
		pn[users]←getpn(ri);
		end;

	line←lookout(prgfile);		! this file gives pn<tab>full name;
	do begin
		string pns;
		rpn←cvsix("   "&(pns←totab(line)));	! sixbit pn;
		for ri ←1 thru users do if rpn=pn[ri] then begin
			name[ri]←left(4,pns)&line;	done;
			end;
		end
	    until ln(line←inline)=0;
	release(inch);
	showjobs;			! print;
	end "RUNNING";

			! main program;
string comm;

ttyup(true);					! upper case input;
backup;	flush(<comm←inchwl>);			! rescan the command;
if "F"≠comm then tosemi(comm) else tonolet(comm);	flush(comm);
print(↓);

if ln(comm)=0 then running else if comm≠"?" then named(comm) else begin "info"
    string ls;
    ls←lookout(docfile);
    do begin print(ls,↓);  ls←inline; end until eof;
    release(inch);
    end "info";
exit;
end "main"
end